home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
IRIX 6.2 Development Libraries
/
SGI IRIX 6.2 Development Libraries.iso
/
dist
/
complib.idb
/
usr
/
share
/
catman
/
p_man
/
cat3
/
complib
/
DCHDD.z
/
DCHDD
Wrap
Text File
|
1996-03-14
|
5KB
|
199 lines
DDDDCCCCHHHHDDDDDDDD((((3333FFFF)))) DDDDCCCCHHHHDDDDDDDD((((3333FFFF))))
NNNNAAAAMMMMEEEE
DCHDD - DCHDD downdates an augmented Cholesky decomposition or the
triangular factor of an augmented QR decomposition. Specifically, given
an upper triangular matrix R of order P, a row vector X, a column vector
Z, and a scalar Y, DCHDD determines an orthogonal matrix U and a scalar
ZETA such that
(R Z ) (RR ZZ)
U * ( ) = ( ) ,
(0 ZETA) ( X Y)
where RR is upper triangular. If R and Z have been obtained from the
factorization of a least squares problem, then RR and ZZ are the factors
corresponding to the problem with the observation (X,Y) removed. In this
case, if RHO is the norm of the residual vector, then the norm of the
residual vector of the downdated problem is DSQRT(RHO**2 - ZETA**2).
DCHDD will simultaneously downdate several triplets (Z,Y,RHO) along with
R. For a less terse description of what DCHDD does and how it may be
applied, see the LINPACK guide.
The matrix U is determined as the product U(1)*...*U(P) where U(I) is a
rotation in the (P+1,I)-plane of the form
( C(I) -S(I) )
( ) .
( S(I) C(I) )
The rotations are chosen so that C(I) is double precision.
The user is warned that a given downdating problem may be impossible to
accomplish or may produce inaccurate results. For example, this can
happen if X is near a vector whose removal will reduce the rank of R.
Beware.
SSSSYYYYNNNNOOOOPPPPSSSSYYYYSSSS
SUBROUTINE DCHDD(R,LDR,P,X,Z,LDZ,NZ,Y,RHO,C,S,INFO)
DDDDEEEESSSSCCCCRRRRIIIIPPPPTTTTIIIIOOOONNNN
On Entry
RRRR DOUBLE PRECISION(LDR,P), where LDR .GE. P.
R contains the upper triangular matrix
that is to be downdated. The part of R
below the diagonal is not referenced.
LLLLDDDDRRRR INTEGER.
LDR is the leading dimension of the array R.
PPPP INTEGER.
P is the order of the matrix R.
PPPPaaaaggggeeee 1111
DDDDCCCCHHHHDDDDDDDD((((3333FFFF)))) DDDDCCCCHHHHDDDDDDDD((((3333FFFF))))
XXXX DOUBLE PRECISION(P).
X contains the row vector that is to
be removed from R. X is not altered by DCHDD.
ZZZZ DOUBLE PRECISION(LDZ,N)Z), where LDZ .GE. P.
Z is an array of NZ P-vectors which
are to be downdated along with R.
LLLLDDDDZZZZ INTEGER.
LDZ is the leading dimension of the array Z.
NNNNZZZZ INTEGER.
NZ is the number of vectors to be downdated
NZ may be zero, in which case Z, Y, and RHO
are not referenced.
YYYY DOUBLE PRECISION(NZ).
Y contains the scalars for the downdating
of the vectors Z. Y is not altered by DCHDD.
RRRRHHHHOOOO DOUBLE PRECISION(NZ).
RHO contains the norms of the residual
vectors that are to be downdated. On Return
RRRR
ZZZZ contain the downdated quantities.
RRRRHHHHOOOO
CCCC DOUBLE PRECISION(P).
C contains the cosines of the transforming
rotations.
SSSS DOUBLE PRECISION(P).
S contains the sines of the transforming
rotations.
IIIINNNNFFFFOOOO INTEGER.
INFO is set as follows.
INFO = 0 if the entire downdating
was successful.
INFO =-1 if R could not be downdated.
in this case, all quantities
are left unaltered.
INFO = 1 if some RHO could not be
downdated. The offending RHO's are
set to -1. LINPACK. This version dated 08/14/78 . Stewart, G. W.,
University of Maryland, Argonne National Lab.
PPPPaaaaggggeeee 2222
DDDDCCCCHHHHDDDDDDDD((((3333FFFF)))) DDDDCCCCHHHHDDDDDDDD((((3333FFFF))))
DDDDCCCCHHHHDDDDDDDD uses the following functions and subprograms. Fortran DABS BLAS
DDOT, DNRM2
PPPPaaaaggggeeee 3333